home *** CD-ROM | disk | FTP | other *** search
/ Libris Britannia 4 / science library(b).zip / science library(b) / PROGRAMM / PASCAL / 0391B.ZIP / INLINE2.ARC / INLINE.PAS < prev   
Pascal/Delphi Source File  |  1986-07-28  |  52KB  |  1,922 lines

  1.                              {Inline16}
  2.  
  3. (*********  Source code Copyright 1986, by L. David Baldwin   *********)
  4.  
  5. {Compiling with mAx=2000 will give sufficient heap for most applications
  6.  and prevent overwriting COMMAND.COM in most cases.}
  7.  
  8. {$v-}
  9. PROGRAM Inline_Asm;
  10.  
  11. const
  12.   CommentColumn = 25;     {column where comments start in object file}
  13.   symbolleng = 32;        {maximum of 32 char symbols}
  14.   cr = 13; lf = 10; tab = 9;
  15.   maxbyte = MaxInt;
  16.   bigstringsize = 127;
  17.  
  18.   signon1 : string[32] =
  19.  
  20.             ^m^j'Inline Assembler, Vers 2.02';
  21.  
  22.   signon2 : string[43] =
  23.  
  24.             ^m^j'(C) Copyright 1986 by L. David Baldwin'^m^j;
  25.  
  26. type
  27.   filestring = string[64];
  28.   symstring = string[symbolleng];
  29.   indxreg = (bx, si, di, bp, none);
  30.   indxset = set of indxreg;
  31.   ptrtype = (bptr, wptr, dwptr, qwptr, tbptr, unkptr); {keep order}
  32.   string4 = string[4];
  33.   string5 = array[1..5] of Char;
  34.   symtype = (address, disp8, disp16, othersym, EOLsym, identifier, jmpdist,
  35.     lfbrack, rtbrack, plus, comma, STsym);
  36.   table = array[0..20] of symstring; {fake}
  37.   bigstring = string[bigstringsize]; {125 chars on a turbo line}
  38.   label_info_ptr = ^label_info;
  39.   label_info = record
  40.                  name : symstring;
  41.                  bytecnt : Integer;
  42.                  next : label_info_ptr;
  43.                end;
  44.   fixup_info_ptr = ^fixup_info;
  45.   fixup_info = record
  46.                  name : symstring;
  47.                  indx, indx2, fix_pt : Integer;
  48.                  jmptype : (short, med);
  49.                  prev, next : fixup_info_ptr;
  50.                end;
  51.  
  52. var
  53.   NoAddrs, aerr, symbol, str_start, TheEnd, st_first : Boolean;
  54.   Addr : Integer;
  55.   sym : symtype;
  56.   modebyt, reg1, reg2, w1, w2, sti_val : Integer;
  57.   displace, wordd, bits_7 : Boolean;
  58.   SaveOfs, DataVal : record
  59.                        symb : Boolean;
  60.                        sname : symstring;
  61.                        value : Integer;
  62.                      end;
  63.   irset : indxset;
  64.   rmm, md : Integer;
  65.   ByWord : ptrtype;
  66.   byt, signext : Byte;
  67.   tindex, tindex0, column, I, ByteCount : Integer;
  68.   TextArray : array[0..maxbyte] of Char;
  69.  
  70.   Lsid : symstring;
  71.   Str8 : array[1..9] of Char; {the following 4 are at the same location}
  72.   Str : string5 absolute Str8;
  73.   id2 : array[1..2] of Char absolute Str8;
  74.   id3 : array[1..3] of Char absolute Str8;
  75.   Uch, Lch : Char;
  76.   Chi, OldChi : Integer;
  77.   out, inn : Text;
  78.  
  79.   start_col : Integer;
  80.   st : bigstring;
  81.   id : string[2];
  82.   firstlabel, pl : label_info_ptr;
  83.   firstfix, pf : fixup_info_ptr;
  84.  
  85. {-------------DefaultExtension}
  86. PROCEDURE DefaultExtension(extension:filestring;VAR infile,name :filestring);
  87. {Given a filename, infile, add a default extension if none exists. Return
  88.  also the name without any extension.}
  89. var
  90.  I,J : Integer;
  91.  temp : filestring;
  92. begin
  93. I:=Pos('..',infile);
  94. if I=0 then
  95.   temp:=infile
  96. else
  97.   {a pathname starting with ..}
  98.   temp:=Copy(infile,I+2,64);
  99. J:=Pos('.',temp);
  100. if J=0 then
  101.   begin
  102.   name := infile;
  103.   infile:=infile+'.'+extension;
  104.   end
  105. else name:=Copy(infile,1,I+J);
  106. end;
  107.  
  108. {-------------Space}
  109. PROCEDURE Space(N : Integer);
  110. var I : Integer;
  111. begin for I := 1 to N do Write(' '); end;
  112.  
  113. {-------------Error}
  114. PROCEDURE Error(ii : Integer; S : bigstring);
  115. var C : Char;
  116. begin
  117. if not aerr then
  118.   begin
  119.   WriteLn(st);
  120.   Space(start_col+ii-4);
  121.   Write('^Error');
  122.   if Length(S) > 0 then
  123.     begin Write(', '); Write(S); end;
  124.   WriteLn;
  125.   aerr := True;
  126.   end;
  127. end;
  128.  
  129. {the following are definitions and variables for the parser}
  130. const
  131. letter : set of Char = ['A'..'Z'];
  132. var segm, nvalue : Integer;
  133. symname : symstring;
  134. {end of parser defs}
  135.  
  136. {-------------GetCh}
  137. PROCEDURE GetCh;
  138.   {return next char in uch and lch with uch in upper case.}
  139. begin
  140. if Chi <= Ord(st[0]) then Lch := st[Chi] else Lch := Chr(cr);
  141. Uch := UpCase(Lch);
  142. Chi := Chi+1;
  143. end;
  144.  
  145. {-------------skipspaces}
  146. PROCEDURE skipspaces;
  147. begin
  148. while (Uch = ' ') or (Uch = Chr(tab)) do GetCh;
  149. end;
  150.  
  151. {-------------getdec}
  152. FUNCTION getdec(var v : Integer) : Boolean;
  153. const ssize = 8;
  154. var
  155.   S : string[ssize];
  156.   getd : Boolean;
  157.   code : Integer;
  158. begin
  159. getd := False;
  160. S := '';
  161. while (Uch >= '0') and (Uch <= '9') do
  162.   begin
  163.   getd := True;
  164.   if Ord(S[0]) < ssize then S := S+Uch;
  165.   GetCh;
  166.   end;
  167. if getd then
  168.   begin
  169.   Val(S, v, code);
  170.   if code <> 0 then Error(Chi, 'Bad number format');
  171.   end;
  172. getdec := getd;
  173. end;
  174.  
  175. {-------------gethex}
  176. FUNCTION gethex(var h : Integer) : Boolean;
  177. var digit : Integer;        {check for '$' before the call}
  178. begin
  179. h := 0; gethex := False;
  180. while (Uch in ['A'..'F', '0'..'9']) do
  181.   begin
  182.   gethex := True;
  183.   if (Uch >= 'A') then digit := Ord(Uch)-Ord('A')+10
  184.     else digit := Ord(Uch)-Ord('0');
  185.   if h >= $1000 then Error(Chi, 'Overflow');
  186.   h := (h shl 4)+digit;
  187.   GetCh;
  188.   end;
  189. end;
  190.  
  191. {-------------getnumber}
  192. FUNCTION getnumber(var N : Integer) : Boolean;
  193.   {get a number and return it in n}
  194. var term : Char;
  195.   err : Boolean;
  196. begin                       {should also handle characters in quotes!!}
  197. N := 0;
  198. if Uch = '(' then GetCh;    {ignore ( }
  199. if (Uch = '''') or (Uch = '"') then
  200.   begin
  201.   term := Uch; GetCh; err := False;
  202.   while (Uch <> term) and not err do
  203.     begin
  204.     err := N and $ff00 <> 0;
  205.     N := (N shl 8)+Ord(Lch);
  206.     GetCh;
  207.     if err then Error(Chi, 'Overflow');
  208.     end;
  209.   GetCh;                    {use up termination char}
  210.   end
  211. else if Uch = '$' then
  212.   begin                     {a hex number}
  213.   GetCh;
  214.   if not gethex(N) then Error(Chi, 'Hex number exp');
  215.   getnumber := True;
  216.   end
  217. else
  218.   getnumber := getdec(N);   {maybe a decimal number}
  219. if Uch = ')' then GetCh;    {ignore an ending parenthesis}
  220. end;
  221.  
  222. {-------------getexpr}
  223. FUNCTION getexpr(var rslt : Integer) : Boolean;
  224. var
  225.   rs1, rs2, SaveChi : Integer;
  226.   Pos, Neg : Boolean;
  227. begin
  228. SaveChi := Chi;
  229. getexpr := False;
  230. skipspaces;
  231. Neg := Uch = '-';
  232. Pos := Uch = '+';
  233. if Pos or Neg then GetCh;
  234. if getnumber(rs1) then
  235.   begin
  236.   getexpr := True;
  237.   if Neg then rs1 := -rs1;
  238.   if (Uch = '+') or (Uch = '-') then
  239.     if getexpr(rs2) then
  240.       rs1 := rs1+rs2;       {getexpr will take care of sign}
  241.   rslt := rs1;
  242.   end
  243. else
  244.   begin
  245.   Chi := SaveChi-1; GetCh;
  246.   end;
  247. end;
  248.  
  249. {$v+}
  250. {-------------getsymbol}
  251. FUNCTION getsymbol(var S : symstring) : Boolean;
  252. const symchars : set of Char = ['A'..'Z', '0'..'9', '_', '+', '-'];
  253. begin
  254. if Uch in letter then
  255.   begin
  256.   getsymbol := True;
  257.   S[0] := Chr(0);
  258.   while Uch in symchars do
  259.     begin
  260.     if Ord(S[0]) < symbolleng then S := S+Uch;
  261.     GetCh;
  262.     end
  263.   end
  264. else getsymbol := False;
  265. end;
  266. {$v-}
  267.  
  268. {-------------getaddress}
  269. FUNCTION getaddress : Boolean;
  270. var result : Boolean;
  271.   SaveChi : Integer;
  272. begin
  273. result := False; SaveChi := Chi;
  274. if getexpr(segm) then
  275.   begin
  276.   skipspaces;
  277.   if Uch = ':' then
  278.     begin
  279.     GetCh; skipspaces;
  280.     result := getexpr(nvalue);
  281.     end;
  282.   end;
  283. getaddress := result;
  284. if not result then
  285.   begin Chi := SaveChi-1; GetCh; end;
  286. end;
  287.  
  288. {-------------errnull}
  289. PROCEDURE errnull;
  290. begin Error(Chi, ''); end;
  291.  
  292. {-------------errincorrect}
  293. PROCEDURE errincorrect;
  294. begin Error(Chi, 'Incorrect or No Operand'); end;
  295.  
  296. {-------------segmerr}
  297. PROCEDURE segmerr;
  298. begin Error(Chi, 'Segm Reg not Permitted'); end;
  299.  
  300. {-------------wordreg}
  301. PROCEDURE wordreg;
  302. begin Error(Chi, 'Word Reg Exp'); end;
  303.  
  304. {-------------datalarge}
  305. PROCEDURE datalarge;
  306. begin Error(Chi, 'Data Too Large'); end;
  307.  
  308. {-------------chk_bwptr}
  309. PROCEDURE chk_bwptr;
  310. begin
  311. if ByWord >= dwptr then Error(Chi, 'BYTE or WORD Req''d');
  312. end;
  313.  
  314. {-------------bytesize}
  315. FUNCTION bytesize(Val : Integer) : Boolean;
  316.   {return true if val is a byte}
  317. begin
  318. bytesize := (Hi(Val) = 0) or (Val and $ff80 = $ff80);
  319. end;
  320.  
  321. {-------------readbyte}
  322. FUNCTION readbyte : Boolean;
  323. var rb : Boolean;
  324. begin
  325. rb := getexpr(nvalue);
  326. if rb then
  327.   if bytesize(nvalue) then
  328.     byt := Lo(nvalue)
  329.   else datalarge;
  330. readbyte := rb;
  331. end;
  332.  
  333. {-------------matchlst}
  334. FUNCTION matchlst(var table; size, maxindx : Integer; var indx : Integer) :
  335.   Boolean;                  {see if str8 matches any string in a table}
  336. var ca : array[0..MaxInt] of Char absolute table;
  337.   rslt : Boolean;
  338.  
  339.   FUNCTION eqarray(var a1; N : Integer) : Boolean;
  340.   type bigarray = array[1..MaxInt] of Char;
  341.   var
  342.     b1 : bigarray absolute a1;
  343.     I : Integer;
  344.   begin
  345.   for I := 1 to N do
  346.     if b1[I] <> Str8[I] then
  347.       begin eqarray := False; Exit; end;
  348.   eqarray := Str8[N+1] = ' '; {must have blank on end for complete match}
  349. end;
  350.  
  351. begin
  352. indx := 0; rslt := False;
  353. while (indx <= maxindx) and not rslt do
  354.   if eqarray(ca[indx*size], size) then
  355.     rslt := True
  356.   else
  357.     indx := indx+1;
  358. matchlst := rslt;
  359. end;
  360.  
  361. {-------------getstring}
  362. PROCEDURE getstring;
  363.   {Fill in lsid, str8, str, id2,id3.  They are, in fact, all in the
  364.    same locations}
  365. var I : Integer;
  366. begin
  367. skipspaces;
  368. Lsid := '          ';
  369. I := 1;
  370. if (Uch >= 'A') and (Uch <= 'Z') then
  371.   begin
  372.   while (Uch >= 'A') and (Uch <= 'Z') or (Uch >= '0') and (Uch <= '9') do
  373.     begin
  374.     if I <= symbolleng then
  375.       begin Lsid[I] := Uch; I := I+1; end;
  376.     GetCh;
  377.     end;
  378.   end;
  379. Lsid[0] := Chr(I-1);
  380. Move(Lsid[1], Str8, 9);     {Fill in str8,str,id2,id3}
  381. end;
  382.  
  383. {-------------InsertChr}
  384. PROCEDURE InsertChr(C : Char);
  385. begin
  386. if tindex <= maxbyte then
  387.   begin
  388.   TextArray[tindex] := C;
  389.   tindex := tindex+1; column := column+1;
  390.   end
  391. else
  392.   begin
  393.   WriteLn('Object Code Overflow!');
  394.   Halt(1);
  395.   end;
  396. end;
  397.  
  398. {-------------InsertStr}
  399. PROCEDURE InsertStr(S : bigstring);
  400. var I : Integer;
  401. begin
  402. for I := 1 to Ord(S[0]) do InsertChr(S[I]);
  403. end;
  404.  
  405. {-------------Hex2}
  406. FUNCTION Hex2(B : Byte) : string4;
  407. const hexdigs : array[0..15] of Char = '0123456789ABCDEF';
  408. var bz : Byte;
  409. begin
  410. bz := B and $f; B := B shr 4;
  411. Hex2 := hexdigs[B]+hexdigs[bz];
  412. end;
  413.  
  414. {-------------Hex4}
  415. FUNCTION Hex4(W : Integer) : string4;
  416. begin Hex4 := Hex2(Lo(W))+Hex2(Hi(W)); end;
  417.  
  418. {-------------InsertByte}
  419. PROCEDURE InsertByte(B : Byte);
  420. begin
  421. if not str_start then InsertChr('/');
  422. InsertStr('$'+Hex2(B));
  423. ByteCount := ByteCount+1;
  424. str_start := False;
  425. end;
  426.  
  427. {-------------InsertWord}
  428. PROCEDURE InsertWord(W : Integer);
  429. begin
  430. InsertByte(Lo(W)); InsertByte(Hi(W));
  431. end;
  432.  
  433. {-------------InsertHi_Low}
  434. PROCEDURE InsertHi_Low(W : Integer);
  435.   {insert a word in reverse order}
  436. begin
  437. InsertByte(Hi(W)); InsertByte(Lo(W));
  438. end;
  439.  
  440. {-------------modify_byte}
  441. PROCEDURE modify_byte(I : Integer; modify : Byte);
  442.   {Modify an ascii byte string in textarray by adding modify to its value}
  443. var
  444.   st : string4;
  445.   J : Integer;
  446.  
  447.   FUNCTION hextobyte(I : Integer; var J : Integer) : Byte;
  448.     {Starting at tindex, i, convert hex to a byte. return j, the tindex where
  449.      byte started}
  450.   var
  451.     result, tmp : Byte;
  452.     C : Char;
  453.   const hex : set of Char = ['0'..'9', 'A'..'F'];
  454.   begin
  455.   result := 0;
  456.   while not(TextArray[I] in hex) do I := I+1; {skip '/' and '$'}
  457.   J := I; C := TextArray[I];
  458.   while C in hex do
  459.     begin
  460.     if C <= '9' then tmp := Ord(C)-Ord('0') else tmp := Ord(C)-Ord('A')+10;
  461.     result := (result shl 4)+tmp;
  462.     I := I+1;
  463.     C := TextArray[I];
  464.     end;
  465.   hextobyte := result;
  466.   end;
  467.  
  468. begin
  469. st := Hex2(hextobyte(I, J)+modify);
  470. TextArray[J] := st[1];
  471. TextArray[J+1] := st[2];
  472. end;
  473.  
  474. {-------------DoNext}
  475. PROCEDURE DoNext;
  476. var I : Integer;
  477.   err : Boolean;
  478.   tmpch : Char;
  479.  
  480. begin
  481. OldChi := Chi;
  482. symbol := False;
  483. if sym = EOLsym then Exit;  {do nothing}
  484. skipspaces;                 {note commas are significant}
  485. if (Uch = Chr(cr)) or (Uch = ';') then sym := EOLsym
  486. else if Uch = ',' then begin sym := comma; GetCh; end
  487. else if (Uch = '>') or (Uch = '<') then
  488.   begin
  489.   tmpch := Uch; GetCh;
  490.   if not getsymbol(symname) then Error(Chi, 'Symbol Name Exp');
  491.   if tmpch = '<' then sym := disp8 else sym := disp16;
  492.   symbol := True;           {disp8/16 is a symbol}
  493.   end
  494. else if getaddress then
  495.   begin
  496.   if NoAddrs then errnull
  497.   else sym := address;
  498.   end
  499. else if getexpr(nvalue) then
  500.   begin
  501.   if bytesize(nvalue) then
  502.     sym := disp8 else sym := disp16;
  503.   end
  504. else if (Uch >= 'A') and (Uch <= 'Z') then
  505.   begin getstring; symname := Lsid;
  506.   if (Lsid = 'FAR') or (Lsid = 'NEAR') or (Lsid = 'SHORT') then
  507.     sym := jmpdist
  508.   else if Lsid = 'ST' then sym := STsym
  509.   else sym := identifier;
  510.   end
  511. else if Uch = '+' then begin sym := plus; GetCh; end
  512. else if Uch = '[' then begin sym := lfbrack; GetCh; end
  513. else if Uch = ']' then begin sym := rtbrack; GetCh; end
  514. else begin sym := othersym; GetCh; end;
  515. end;
  516.  
  517. {-------------NextA}
  518. PROCEDURE NextA;            {Get the next item but also process any
  519.                             'WORD' 'BYTE', 'DWORD', 'QWORD',etc 'PTR'}
  520. type sizeary = array[0..4] of string[2];
  521. var tmp : ptrtype;
  522.   indx : Integer;
  523. const ptrary : sizeary = ('BY', 'WO', 'DW', 'QW', 'TB');
  524.       ptrary1 : array[0..4] of string[5] =
  525.                   ('BYTE','WORD','DWORD','QWORD','TBYTE');
  526.  
  527. begin
  528. DoNext;
  529. if sym = identifier then
  530.   begin
  531.   tmp := bptr; indx := 0;
  532.   while (tmp < unkptr) and (Lsid <> ptrary[indx]) and (Lsid <>ptrary1[indx]) do
  533.     begin
  534.     tmp := Succ(tmp); indx := indx+1;
  535.     end;
  536.   if tmp < unkptr then
  537.     begin ByWord := tmp; DoNext; end;
  538.   if Str = 'PTR  ' then DoNext; {ignore 'PTR'}
  539.   end;
  540. end;
  541.  
  542. {-------------displace_bytes}
  543. PROCEDURE displace_bytes(W : Integer);
  544. var C : Char;
  545. begin
  546. if displace then
  547.   with SaveOfs do
  548.     if symb then
  549.       begin                 {displacement is a symbol}
  550.       if W = 1 then C := '>' else C := '<';
  551.       InsertStr('/'+C+sname);
  552.       if value <> 0 then    {Add it in too, don't reverse bytes}
  553.         InsertStr('+$'+Hex2(Hi(value))+Hex2(Lo(value)));
  554.       if W = 1 then ByteCount := ByteCount+2 else ByteCount := ByteCount+1;
  555.       end
  556.     else begin
  557.     if W = 1 then InsertWord(value) else InsertByte(Lo(value));
  558.     end;
  559. end;
  560.  
  561. {-------------data_bytes}
  562. PROCEDURE data_bytes(word : Boolean);
  563. var C : Char;
  564. begin
  565. with DataVal do
  566.   if symb then
  567.     begin                   {data is a symbol}
  568.     if word then C := '>' else C := '<';
  569.     InsertStr('/'+C+sname);
  570.     if value <> 0 then      {add it in too}
  571.       InsertStr('+$'+Hex2(Hi(value))+Hex2(Lo(value)));
  572.     if word then ByteCount := ByteCount+2 else ByteCount := ByteCount+1;
  573.     end
  574.   else begin
  575.   if word then InsertWord(value) else InsertByte(Lo(value));
  576.   end;
  577. end;
  578.  
  579. {-------------GetIR}
  580. FUNCTION GetIR : Boolean;
  581. var reg : indxreg;
  582. begin
  583. GetIR := False; reg := none;
  584. if (sym = identifier) and (Lsid[0] = Chr(2)) then
  585.   if id2 = 'BX' then reg := bx
  586.   else if id2 = 'SI' then reg := si
  587.   else if id2 = 'DI' then reg := di
  588.   else if id2 = 'BP' then reg := bp;
  589. if reg <> none then
  590.   begin
  591.   irset := irset+[reg];
  592.   GetIR := True;
  593.   NextA;
  594.   end;
  595. end;
  596.  
  597. {-------------MemReg}
  598. FUNCTION MemReg(var W : Integer) : Boolean;
  599. label 10;
  600.  
  601.   {Does not handle the 'reg' part of the mem/reg. Returns disp true if
  602.   a displacement is found with w=0 for byte disp and w=1 for word
  603.   disp.  Any displacement is output in saveofs.}
  604.  
  605. var
  606.   SaveChi : Integer;
  607.   dsp16, oldaddrs, result_MemReg : Boolean;
  608. begin
  609. SaveChi := OldChi; dsp16 := False;
  610. result_MemReg := False;
  611. oldaddrs := NoAddrs; NoAddrs := True;
  612. SaveOfs.value := 0; SaveOfs.symb := False; irset := [];
  613. while (sym <> comma) and (sym <> EOLsym) do {',' or cr terminate a MemReg}
  614.   begin
  615.   if sym = lfbrack then
  616.     begin result_MemReg := True; NextA; end;
  617.   if sym = plus then NextA;
  618.   if (sym = disp8) or (sym = disp16) then
  619.     with SaveOfs do
  620.       begin
  621.       dsp16 := dsp16 or (sym = disp16);
  622.       if symbol then
  623.         begin
  624.         symb := True; sname := symname;
  625.         end
  626.       else value := value+nvalue;
  627.       NextA;
  628.       end
  629.   else if not GetIR then
  630.     if sym = rtbrack then NextA
  631.     else if result_MemReg then
  632.       begin Error(Chi, 'Comma or Line End Exp'); NextA; end
  633.     else goto 10;           {abort}
  634.   end;
  635. if result_MemReg then
  636.   begin                     {at least one '[' found}
  637.   if (irset = []) or (irset = [bp]) then rmm := 6
  638.   else if irset = [bx, si] then rmm := 0
  639.   else if irset = [bx, di] then rmm := 1
  640.   else if irset = [bp, si] then rmm := 2
  641.   else if irset = [bp, di] then rmm := 3
  642.   else if irset = [si] then rmm := 4
  643.   else if irset = [di] then rmm := 5
  644.   else if irset = [bx] then rmm := 7
  645.   else Error(Chi, 'Bad Register Combination');
  646.  
  647.   NextA;                    {pass over any commas}
  648.   with SaveOfs do
  649.     dsp16 := dsp16 or (symb and (value <> 0)) or not bytesize(value);
  650.   if irset = [] then
  651.     begin displace := True; md := 0; W := 1; end {direct address}
  652.   else if (irset = [bp]) and not dsp16 then
  653.     begin displace := True; md := 1; W := 0; end {bp must have displ}
  654.   else if (SaveOfs.value = 0) and not SaveOfs.symb then
  655.     begin displace := False; md := 0; W := 3; end
  656.   else if not dsp16 then    {8 bit}
  657.     begin displace := True; md := 1; W := 0; end
  658.   else begin displace := True; md := 2; W := 1; end;
  659.   modebyt := 64*md+rmm;
  660.   end
  661. else
  662. 10: begin                     {not a MemReg}
  663.   Chi := SaveChi-1; GetCh;  {restore as in beginning}
  664.   NextA;
  665.   end;
  666. NoAddrs := oldaddrs;
  667. MemReg := result_MemReg;
  668. end;
  669.  
  670. {-------------st_st}
  671. FUNCTION st_st : Boolean;   {pick up st,st(i) or st(i),st or just st(i)}
  672. var err, rslt : Boolean;
  673.  
  674.   FUNCTION getsti_val : Boolean;
  675.   var grslt : Boolean;
  676.   begin
  677.   NextA;
  678.   grslt := sym = disp8;
  679.   if grslt then
  680.     begin
  681.     sti_val := nvalue;
  682.     err := ((sti_val and $f8) <> 0); {check limit of 7}
  683.     NextA;
  684.     end;
  685.   getsti_val := grslt;
  686.   end;
  687.  
  688. begin
  689. err := False;
  690. rslt := sym = STsym;
  691. if rslt then
  692.   begin
  693.   if getsti_val then
  694.     begin
  695.     st_first := False;      {st(i) is first}
  696.     while (sym = comma) or (sym = STsym) do NextA;
  697.     end
  698.   else
  699.     begin
  700.     st_first := True;       {st preceeds st(i)}
  701.     if sym = comma then NextA;
  702.     if sym = STsym then
  703.       begin
  704.       if not getsti_val then
  705.         err := True;
  706.       end
  707.     else err := True;
  708.     end;
  709.   if err then errnull;
  710.   end;
  711. st_st := rslt;
  712. end;
  713.  
  714. {-------------fstionly}
  715. FUNCTION fstionly : Boolean;
  716.   {Fl Pt instructions having only one form using st(i) operand}
  717.   {faddp,fmulp,fsubp,fsubrp,fdivp,fdivrp,ffree,fxch -- 0..7 }
  718. type arraytype = array[0..7] of Integer;
  719.   table = array[0..7, 0..5] of Char;
  720. var indx : Integer;
  721.   rslt : Boolean;
  722. const
  723.   stiary : arraytype =
  724.        ($dec0, $dec8, $dee8, $dee0, $def8, $def0, $ddc0, $d9c8);
  725.   stionlytable : table = ('FADDP ', 'FMULP ', 'FSUBP ',
  726.        'FSUBRP', 'FDIVP ', 'FDIVRP', 'FFREE ', 'FXCH  ');
  727.  
  728. begin
  729. rslt := matchlst(stionlytable, 6, 7, indx);
  730. if rslt then
  731.   begin
  732.   NextA;
  733.   if not st_st then
  734.     begin
  735.     if sym = EOLsym then sti_val := 1
  736.     else errincorrect;
  737.     end;
  738.   InsertByte($9b);
  739.   InsertHi_Low(stiary[indx]+sti_val);
  740.   end;
  741. fstionly := rslt;
  742. end;
  743.  
  744. {-------------fmemonly}
  745. FUNCTION fmemonly : Boolean;
  746.   {Fl Pt instructions having only one form using a memory operand}
  747.   {fldenv,fldcw,fstenv,fstcw,fbstp,fbld,frstor,fsave,fstsw,
  748.   fnsave,fnstcw,fnstenv,fnstsw--0..12 }
  749. type arraytype = array[0..12] of Integer;
  750.   table = array[0..12, 0..6] of Char;
  751. var indx : Integer;
  752.   rslt : Boolean;
  753. const
  754.   memary : arraytype = (
  755.     $d920, $d928, $d930, $d938, $df30, $df20, $dd20, $dd30, $dd38,
  756.     $dd30, $d938, $d930, $dd38);
  757.   memonlytable : table =
  758.    ('FLDENV ', 'FLDCW  ', 'FSTENV ', 'FSTCW  ', 'FBSTP  ', 'FBLD   ',
  759.     'FRSTOR ', 'FSAVE  ', 'FSTSW  ',
  760.     'FNSAVE ', 'FNSTCW ', 'FNSTENV', 'FNSTSW ');
  761. begin
  762. rslt := matchlst(memonlytable, 7, 12, indx);
  763. if rslt then
  764.   begin
  765.   NextA;
  766.   if indx < 9 then InsertByte($9b); {fwait}
  767.   if MemReg(w1) then
  768.     begin
  769.     InsertHi_Low(memary[indx]+modebyt);
  770.     displace_bytes(w1);
  771.     end
  772.   else errincorrect;
  773.   end;
  774. fmemonly := rslt;
  775. end;
  776.  
  777. {-------------fldtype}
  778. FUNCTION fldtype : Boolean;
  779.   {Do fld,fst,fstp-- 0..2}
  780. type
  781.   arraytype = array[0..2, dwptr..unkptr] of Integer;
  782.   table = array[0..2, 0..3] of Char;
  783. var indx, tmp : Integer;
  784.   rslt : Boolean;
  785. const
  786.   fldarray : arraytype = (
  787.     ($d900, $dd00, $db28, $d9c0),
  788.     ($d910, $dd10, 0, $ddd0),
  789.     ($d918, $dd18, $db38, $ddd8));
  790.   fldtable : table = ('FLD ', 'FST ', 'FSTP');
  791. begin
  792. rslt := matchlst(fldtable, 4, 2, indx);
  793. if rslt then
  794.   begin
  795.   NextA;
  796.   InsertByte($9b);           {fwait}
  797.   if ByWord >= dwptr then
  798.     tmp := fldarray[indx, ByWord];
  799.   if MemReg(w1) then
  800.     begin
  801.     if (ByWord >= dwptr) and (ByWord <= tbptr) then
  802.       begin
  803.       InsertHi_Low(tmp+modebyt);
  804.       displace_bytes(w1);
  805.       if tmp = 0 then Error(Chi, 'TBYTE not Permitted');
  806.       end
  807.     else Error(Chi, 'DWORD, QWORD, or TBYTE Req''d');
  808.     end
  809.   else if st_st then
  810.     InsertHi_Low(tmp+sti_val)
  811.   else errincorrect;
  812.   end;
  813. fldtype := rslt;
  814. end;
  815.  
  816. {-------------fildtype}
  817. FUNCTION fildtype : Boolean;
  818.   {do fild,fist,fistp-- 0..2}
  819. type
  820.   arraytype = array[0..2, wptr..qwptr] of Integer;
  821.   table = array[0..2, 0..4] of Char;
  822. var indx, tmp : Integer;
  823.   rslt : Boolean;
  824. const
  825.   fildarray : arraytype = (
  826.     ($df00, $db00, $df28),
  827.     ($df10, $db10, 0),
  828.     ($df18, $db18, $df38));
  829.   fildtable : table = ('FILD ', 'FIST ', 'FISTP');
  830. begin
  831. rslt := matchlst(fildtable, 5, 2, indx);
  832. if rslt then
  833.   begin
  834.   NextA;
  835.   if MemReg(w1) then
  836.     begin
  837.     if (ByWord >= wptr) and (ByWord <= qwptr) then
  838.       begin
  839.       InsertByte($9b);       {fwait}
  840.       tmp := fildarray[indx, ByWord];
  841.       InsertHi_Low(tmp+modebyt);
  842.       displace_bytes(w1);
  843.       if tmp = 0 then Error(Chi, 'QWORD not Permitted');
  844.       end
  845.     else Error(Chi, 'WORD, DWORD, or QWORD Req''d');
  846.     end
  847.   else errincorrect;
  848.   end;
  849. fildtype := rslt;
  850. end;
  851.  
  852. {-------------faddtype}
  853. FUNCTION faddtype : Boolean;
  854.   {The fadd,fmul,fcom,fcomp,fsub,fsubr,fdiv,fdivr instructions}
  855. var indx : Integer;
  856.   rslt : Boolean;
  857. type table = array[0..7, 0..4] of Char;
  858. const faddtable : table = ('FADD ', 'FMUL ', 'FCOM ', 'FCOMP',
  859.   'FSUB ', 'FSUBR', 'FDIV ', 'FDIVR');
  860. begin
  861. rslt := False;
  862. if matchlst(faddtable, 5, 7, indx) then
  863.   begin
  864.   NoAddrs := True;
  865.   rslt := True;
  866.   NextA;
  867.   InsertByte($9b);           {fwait}
  868.   if MemReg(w1) then
  869.     begin
  870.     if ByWord = dwptr then InsertByte($d8)
  871.     else if ByWord = qwptr then InsertByte($dc)
  872.     else Error(Chi, 'DWORD or QWORD Req''d');
  873.     InsertByte(modebyt+8*indx);
  874.     displace_bytes(w1);
  875.     end
  876.   else if st_st then        {Must be st,st(i) or st(i),st }
  877.     begin
  878.     if st_first or (indx = 2 {fcom} ) or (indx = 3 {fcomp} ) then
  879.     InsertByte($d8) else InsertByte($dc);
  880.     modebyt := $c0+8*indx+sti_val;
  881.     if not st_first and (indx >= 6 {fdiv} ) then
  882.       modebyt := modebyt xor 8; {reverse fdiv,fdivr for not st_first}
  883.     InsertByte(modebyt);
  884.     end
  885.   else errincorrect;
  886.   end;
  887. faddtype := rslt;
  888. end;
  889.  
  890. {-------------fiaddtype}
  891. FUNCTION fiaddtype : Boolean;
  892.   {the fiadd,fimul,ficom,ficomp,fisub,fisubr,fidiv,fidivr instructions}
  893. type table = array[0..7, 0..5] of Char;
  894. var indx : Integer;
  895.   rslt : Boolean;
  896. const fiaddtable : table = ('FIADD ', 'FIMUL ', 'FICOM ', 'FICOMP',
  897.   'FISUB ', 'FISUBR', 'FIDIV ', 'FIDIVR');
  898. begin
  899. rslt := False;
  900. if matchlst(fiaddtable, 6, 7, indx) then
  901.   begin
  902.   NoAddrs := True;
  903.   rslt := True;
  904.   NextA;
  905.   if MemReg(w1) then
  906.     begin
  907.     InsertByte($9b);         {fwait}
  908.     if ByWord = dwptr then InsertByte($da)
  909.     else if ByWord = wptr then InsertByte($de)
  910.     else Error(Chi, 'WORD or DWORD Req''d');
  911.     InsertByte(modebyt+8*indx);
  912.     displace_bytes(w1);
  913.     end
  914.   else errincorrect;
  915.   end;
  916. fiaddtype := rslt;
  917. end;
  918.  
  919. {-------------fnoperand}
  920. FUNCTION fnoperand : Boolean;
  921.   {do the Fl Pt no operand instructions}
  922. type table = array[0..32, 0..6] of Char;
  923. var indx : Integer;
  924.   rslt : Boolean;
  925. const
  926.   fnoptable : table =       {Ordered with fnopcode}
  927.    ('FNOP   ', 'FCHS   ', 'FABS   ', 'FTST   ', 'FXAM   ',
  928.     'FLD1   ', 'FLDL2T ', 'FLDL2E ', 'FLDPI  ', 'FLDLG2 ', 'FLDLN2 ',
  929.     'FLDZ   ', 'F2XM1  ', 'FYL2X  ', 'FPTAN  ', 'FPATAN ', 'FXTRACT',
  930.     'FDECSTP', 'FINCSTP', 'FPREM  ', 'FYL2XP1', 'FSQRT  ', 'FRNDINT',
  931.     'FSCALE ', 'FENI   ', 'FDISI  ', 'FCLEX  ', 'FINIT  ', 'FCOMPP ',
  932.     'FNCLEX ', 'FNDISI ', 'FNENI  ', 'FNINIT ');
  933.  
  934.   fnopcode : array[0..32] of Integer =
  935.    ($d9d0, $d9e0, $d9e1, $d9e4, $d9e5, $d9e8,
  936.     $d9e9, $d9ea, $d9eb, $d9ec, $d9ed, $d9ee,
  937.     $d9f0, $d9f1, $d9f2, $d9f3, $d9f4, $d9f6,
  938.     $d9f7, $d9f8, $d9f9, $d9fa, $d9fc, $d9fd,
  939.     $dbe0, $dbe1, $dbe2, $dbe3, $ded9,
  940.     $dbe2, $dbe1, $dbe0, $dbe3);
  941.  
  942. begin
  943. rslt := matchlst(fnoptable, 7, 32, indx);
  944. if rslt then
  945.   begin
  946.   NextA;
  947.   if indx < 29 then InsertByte($9b); {fwait}
  948.   InsertHi_Low(fnopcode[indx]);
  949.   end;
  950. fnoperand := rslt;
  951. end;
  952.  
  953. {-------------register}
  954. FUNCTION register(var R, W : Integer) : Boolean;
  955. type
  956.   regarytype = array[0..15] of array[1..2] of Char;
  957. const regarray : regarytype = (
  958.   'AL', 'CL', 'DL', 'BL', 'AH', 'CH', 'DH', 'BH',
  959.   'AX', 'CX', 'DX', 'BX', 'SP', 'BP', 'SI', 'DI');
  960. var result_reg : Boolean;
  961. begin
  962. result_reg := False;
  963. if (Lsid[0] = Chr(2)) and (sym = identifier) then
  964.   begin
  965.   R := $ffff;
  966.   repeat
  967.     R := R+1;
  968.   until (R > 15) or (id2 = regarray[R]);
  969.   result_reg := R <= 15;
  970.   if result_reg then
  971.     begin
  972.     NextA;
  973.     if sym = comma then NextA;
  974.     end;
  975.   W := R div 8;             {w=1 for word type register}
  976.   R := R and 7;
  977.   end;
  978. register := result_reg;
  979. end;
  980.  
  981. {-------------segregister}
  982. FUNCTION segregister(var R : Integer) : Boolean;
  983. var result_segr : Boolean;
  984. begin
  985. if (sym = identifier) and (Lsid[0] = Chr(2)) then
  986.   begin
  987.   result_segr := True;
  988.   if id2 = 'ES' then R := 0
  989.   else if id2 = 'CS' then R := 1
  990.   else if id2 = 'SS' then R := 2
  991.   else if id2 = 'DS' then R := 3
  992.   else result_segr := False;
  993.   if result_segr then
  994.     begin
  995.     NextA;
  996.     if sym = comma then NextA;
  997.     end;
  998.   end
  999. else result_segr := False;
  1000. segregister := result_segr;
  1001. end;
  1002.  
  1003. {-------------Data}
  1004. FUNCTION Data(var wd : Boolean) : Boolean;
  1005.   {See if immediate data is present.  Set wd if data found is word size}
  1006. var SaveChi : Integer;
  1007.   result : Boolean;
  1008. begin
  1009. result := False; wd := False;
  1010. SaveChi := OldChi;
  1011. with DataVal do
  1012.   begin
  1013.   value := 0; symb := False;
  1014.   while (sym = disp8) or (sym = disp16) do
  1015.     begin
  1016.     result := True;
  1017.     if symbol then
  1018.       begin
  1019.       wd := wd or (sym = disp16);
  1020.       symb := True;
  1021.       sname := symname;
  1022.       end
  1023.     else value := value+nvalue;
  1024.     NextA; if sym = plus then NextA;
  1025.     end;
  1026.   result := (sym = EOLsym) and result;
  1027.   wd := wd or not bytesize(value);
  1028.   end;
  1029. Data := result;
  1030. if not result then
  1031.   begin
  1032.   Chi := SaveChi-1; GetCh; NextA;
  1033.   end;
  1034. end;
  1035.  
  1036. {-------------TwoOperands}
  1037. FUNCTION TwoOperands : Boolean;
  1038.   {Handles codes with two operands}
  1039. label 2;
  1040. type instype = (mov, adc, addx, andx, cmp, orx, sbb, sub, xorx, test, xchg,
  1041.   lds, les, lea);
  1042.   nametype = array[mov..lea] of array[1..5] of Char;
  1043.   codetype = array[mov..lea] of Byte;
  1044.   shcodetype = array[mov..test] of Byte;
  1045. var inst : instype;
  1046.   tmp : Byte;
  1047.  
  1048. const instname : nametype = (
  1049.   'MOV  ', 'ADC  ', 'ADD  ', 'AND  ', 'CMP  ', 'OR   ',
  1050.   'SBB  ', 'SUB  ', 'XOR  ', 'TEST ', 'XCHG ', 'LDS  ',
  1051.   'LES  ', 'LEA  ');
  1052.  
  1053.   immedop : codetype = ($c6, $80, $80, $80, $80, $80, $80, $80, $80, $f6, 0,
  1054.     0, 0, 0);
  1055.   immedreg : codetype = (0, $10, 0, $20, $38, 8, $18, $28, $30, 0, 0,
  1056.     0, 0, 0);
  1057.   memregop : codetype = ($88, $10, 0, $20, $38, 8, $18, $28, $30, $84, $86,
  1058.     $c5, $c4, $8d);
  1059.   shimmedop : shcodetype = (0, $14, 4, $24, $3c, $c, $1c, $2c, $34, $a8);
  1060.  
  1061. begin TwoOperands := False;
  1062. for inst := mov to lea do
  1063.   if Str = instname[inst] then
  1064.     goto 2;
  1065. Exit;                         {not found}
  1066. 2:                            {found}
  1067. NoAddrs := True;            {full address not acceptable}
  1068. TwoOperands := True;
  1069. NextA;
  1070. if register(reg1, w1) then
  1071.   begin
  1072.   if register(reg2, w2) then
  1073.     begin                   {mov reg,reg}
  1074.     if inst >= lds then Error(Chi, 'Register not Permitted');
  1075.     if w1 <> w2 then Error(Chi, 'Registers Incompatible');
  1076.     if (inst = xchg) and ((w1 = 1) and ((reg1 = 0) or (reg2 = 0))) then
  1077.       InsertByte($90+reg1+reg2)
  1078.     else
  1079.       begin
  1080.       InsertByte(memregop[inst]+w1);
  1081.       InsertByte($c0+reg1+8*reg2);
  1082.       end;
  1083.     end
  1084.   else if segregister(reg2) then
  1085.     begin                   {mov reg,segreg}
  1086.     if (w1 = 0) or (inst <> mov) then segmerr;
  1087.     InsertByte($8c); InsertByte($c0+8*reg2+reg1);
  1088.     end
  1089.   else if Data(wordd) then
  1090.     begin                   {mov reg,data}
  1091.     signext := 0;           {signext not presently in use}
  1092.     if inst >= xchg then Error(Chi, 'Immediate not Permitted');
  1093.     if (Ord(wordd) > w1) then datalarge;
  1094.     if (inst = mov) then
  1095.       begin
  1096.       InsertByte($b0+8*w1+reg1);
  1097.       end
  1098.     else
  1099.       if (reg1 = 0) {ax or al} then
  1100.         InsertByte(shimmedop[inst]+w1) {add ac,immed}
  1101.       else
  1102.         begin
  1103.         (*       if (inst<>test) and (w1=1) and bits_7 then
  1104.         signext:=2;         {the sign extension bit}     *)
  1105.         InsertByte(immedop[inst]+w1+signext);
  1106.         InsertByte($c0+immedreg[inst]+reg1);
  1107.         end;
  1108.     (*    Insertbyte(lo(dataval));
  1109.     if (w1>0) and (signext=0) then Insertbyte(hi(dataval));   *)
  1110.     data_bytes(w1 > 0);     {output the immediate data}
  1111.     end
  1112.   else if MemReg(w2) then
  1113.     begin                   {mov reg,mem/reg}
  1114.     if (inst = mov) and (reg1 = 0) {ax or al} and (rmm = 6) and (md = 0) then
  1115.       begin                 {mov ac,mem}
  1116.       InsertByte($a0+w1);
  1117.       end
  1118.     else
  1119.       begin
  1120.       tmp := memregop[inst];
  1121.       if inst <= xchg then
  1122.         begin
  1123.         tmp := tmp+w1;
  1124.         if inst <> test then tmp := tmp or 2; {to,from bit}
  1125.         end;
  1126.       InsertByte(tmp);
  1127.       InsertByte(modebyt+8*reg1);
  1128.       end;
  1129.     displace_bytes(w2);     {add on any displacement bytes}
  1130.     end
  1131.   else errnull;
  1132.   end
  1133. else if segregister(reg1) then
  1134.   begin
  1135.   if inst <> mov then segmerr;
  1136.   InsertByte($8e);
  1137.   if register(reg2, w2) then
  1138.     begin                   {mov segreg,reg}
  1139.     if (w2 = 0) then wordreg;
  1140.     InsertByte($c0+8*reg1+reg2);
  1141.     end
  1142.   else if MemReg(w2) then
  1143.     begin                   {mov segreg,mem/reg}
  1144.     InsertByte(modebyt+8*reg1);
  1145.     displace_bytes(w2);     {add any displacement bytes}
  1146.     end
  1147.   else errnull;
  1148.   end
  1149. else if MemReg(w1) and (inst <= xchg) then
  1150.   begin
  1151.   if register(reg2, w2) then
  1152.     begin                   {mov mem/reg,reg}
  1153.     if (w2 > Ord(ByWord)) then Error(Chi, 'Byte Reg Exp');
  1154.     if (inst = mov) and (reg2 = 0) {ax or al} and (rmm = 6) and (md = 0) then
  1155.       begin                 {mov ac, mem}
  1156.       InsertByte($a2+w2);
  1157.       end
  1158.     else
  1159.       begin
  1160.       InsertByte(memregop[inst]+w2);
  1161.       InsertByte(modebyt+8*reg2);
  1162.       end;
  1163.     displace_bytes(w1);
  1164.     end
  1165.   else if segregister(reg2) then
  1166.     begin                   {mov mem/reg,segreg}
  1167.     if (inst <> mov) then segmerr;
  1168.     InsertByte($8c); InsertByte(modebyt+8*reg2);
  1169.     displace_bytes(w1);
  1170.     end
  1171.   else if (Data(wordd)) and (inst < xchg) then
  1172.     begin                   {mov mem/reg, data}
  1173.     chk_bwptr;
  1174.     if (Ord(wordd) > Ord(ByWord)) then datalarge;
  1175.     (*     if (inst>=adc) and (inst<=xorx) and (byword=wptr) and bits_7 then
  1176.     signext:=2 else *) signext := 0; {the sign extension bit,
  1177.                                        not currently used}
  1178.     InsertByte(immedop[inst]+Ord(ByWord)+signext);
  1179.     InsertByte(modebyt+immedreg[inst]);
  1180.     displace_bytes(w1);     {add displacement bytes}
  1181.     (*     Insertbyte(lo(dataval));
  1182.     if (byword=wptr) and (signext=0) then Insertbyte(hi(dataval));  *)
  1183.     data_bytes(ByWord = wptr); {the immediate data}
  1184.     end
  1185.   else errnull;
  1186.   end
  1187. else if (sym = disp8) or (sym = disp16) then
  1188.   Error(Chi, 'Immediate not Permitted')
  1189. else errnull;
  1190. end;
  1191.  
  1192. {-------------OneOperand}
  1193. FUNCTION OneOperand : Boolean;
  1194.   {Handles codes with one operand}
  1195. type instype = (dec, inc, push, pop, nott, Neg);
  1196.   nametype = array[dec..Neg] of array[1..5] of Char;
  1197.   codetype = array[dec..Neg] of Byte;
  1198. var inst : instype;
  1199.   pushpop : Boolean;
  1200.  
  1201. const
  1202.   instname : nametype = (
  1203.      'DEC  ', 'INC  ', 'PUSH ', 'POP  ', 'NOT  ', 'NEG  ');
  1204.  
  1205.   regop : codetype = ($48, $40, $50, $58, 0, 0);
  1206.   segregop : codetype = (0, 0, 6, 7, 0, 0);
  1207.   memregop : codetype = ($fe, $fe, $ff, $8f, $f6, $f6);
  1208.   memregcode : codetype = ($8, 0, $30, 0, $10, $18);
  1209.  
  1210. begin OneOperand := False;
  1211. for inst := dec to Neg do
  1212.   if Str = instname[inst] then
  1213.     begin
  1214.     pushpop := (inst = push) or (inst = pop);
  1215.     NoAddrs := True;
  1216.     OneOperand := True;
  1217.     NextA;
  1218.     if register(reg1, w1) then
  1219.       begin
  1220.       if (w1 = 1) and (inst < nott) then
  1221.         begin               {16 bit register instructions}
  1222.         InsertByte(regop[inst]+reg1);
  1223.         end
  1224.       else begin            {byte register or neg,not with any reg}
  1225.       InsertByte(memregop[inst]+w1);
  1226.       InsertByte($c0+memregcode[inst]+reg1);
  1227.       if pushpop then
  1228.         wordreg;
  1229.       end
  1230.       end                   {if reg}
  1231.     else if segregister(reg1) then
  1232.       begin                 {segment reg--push,pop only}
  1233.       InsertByte(segregop[inst]+8*reg1);
  1234.       if not pushpop then segmerr
  1235.       end
  1236.     else if MemReg(w1) then
  1237.       begin                 {memreg  (not register)}
  1238.       if not pushpop then chk_bwptr;
  1239.       InsertByte(memregop[inst] or Ord(ByWord));
  1240.       InsertByte(modebyt+memregcode[inst]);
  1241.       displace_bytes(w1);
  1242.       end
  1243.     else errincorrect;
  1244.     end;                    {if st}
  1245. end;
  1246.  
  1247. {-------------NoOperand}
  1248. FUNCTION NoOperand : Boolean;
  1249.   {Those instructions consisting only of opcode}
  1250. const nmbsop = 31;
  1251. type sofield = array[0..nmbsop] of array[1..5] of Char;
  1252.   opfield = array[0..nmbsop] of Byte;
  1253. var index : Integer;
  1254. const
  1255.   sop : sofield = (
  1256.     'DAA  ', 'AAA  ', 'NOP  ', 'MOVSB', 'MOVSW', 'CMPSB', 'CMPSW',
  1257.     'XLAT ', 'HLT  ',
  1258.     'CMC  ', 'DAS  ', 'AAS  ', 'CBW  ', 'CWD  ', 'PUSHF',
  1259.     'POPF ', 'SAHF ', 'LAHF ', 'STOSB', 'STOSW', 'LODSB', 'LODSW',
  1260.     'SCASB', 'SCASW', 'INTO ', 'IRET ', 'CLC  ', 'STC  ', 'CLI  ',
  1261.     'STI  ', 'CLD  ', 'STD  ');
  1262.   opcode : opfield = (
  1263.     $27, $37, $90, $a4, $a5, $a6, $a7, $d7, $f4,
  1264.     $f5, $2f, $3f, $98, $99, $9c, $9d, $9e, $9f, $aa, $ab, $ac, $ad,
  1265.     $ae, $af, $ce, $cf, $f8, $f9, $fa, $fb, $fc, $fd);
  1266.  
  1267. begin NoOperand := False;
  1268. for index := 0 to nmbsop do
  1269.   if Str = sop[index] then
  1270.     begin
  1271.     InsertByte(opcode[index]);
  1272.     NoOperand := True;
  1273.     NextA;
  1274.     Exit;
  1275.     end;
  1276. end;
  1277.  
  1278. {-------------prefix}
  1279. FUNCTION prefix : Boolean;
  1280.   {process the prefix instructions}
  1281. const nmbsop = 11;
  1282. type field = array[0..nmbsop] of string5;
  1283.   opfield = array[0..nmbsop] of Byte;
  1284. var index : Integer;
  1285. const
  1286.   ops : field = (
  1287.     'LOCK ', 'REP  ', 'REPZ ',
  1288.     'REPNZ', 'REPE ', 'REPNE', 'WAIT ', 'FWAIT',
  1289.     'ES   ', 'DS   ', 'CS   ', 'SS   ');
  1290.   opcode : opfield = (
  1291.     $f0, $f2, $f3, $f2, $f3, $f2, $9b, $9b, $26, $3e, $2e, $36);
  1292.  
  1293. begin prefix := False;
  1294. for index := 0 to nmbsop do
  1295.   if Str = ops[index] then
  1296.     begin
  1297.     InsertByte(opcode[index]);
  1298.     tindex0 := tindex;      {for future fix ups}
  1299.     if Uch = ':' then GetCh; {es: etc permitted with a colon}
  1300.     prefix := True;
  1301.     Exit;
  1302.     end;
  1303. end;
  1304.  
  1305. {-------------FindLabel}
  1306. FUNCTION FindLabel(var B : Integer) : Boolean;
  1307.   {Find a label if it exists in the label chain}
  1308. var found : Boolean;
  1309. begin
  1310. pl := firstlabel; found := False;
  1311. while (pl <> nil) and not found do
  1312.   with pl^ do
  1313.     if symname = name then
  1314.       begin
  1315.       found := True;
  1316.       B := bytecnt;
  1317.       end
  1318.     else pl := next;
  1319. FindLabel := found;
  1320. end;
  1321.  
  1322. {-------------shortjmp}
  1323. FUNCTION shortjmp : Boolean;
  1324.   {short jump instructions}
  1325. const numjmp = 34;
  1326. type
  1327.   sjfield = array[0..numjmp] of array[1..5] of Char;
  1328.   opfield = array[0..numjmp] of Byte;
  1329. var I, B : Integer;
  1330. const
  1331.   jumps : sjfield = (
  1332.     'JO   ', 'JNO  ', 'JB   ', 'JNAE ', 'JNB  ', 'JAE  ',
  1333.     'JE   ', 'JZ   ', 'JNE  ', 'JNZ  ', 'JBE  ', 'JNA  ',
  1334.     'JNBE ', 'JA   ', 'LOOPN', 'LOOPZ', 'LOOPE', 'LOOP ',
  1335.     'JCXZ ', 'JS   ', 'JNS  ', 'JP   ', 'JPE  ', 'JNP  ',
  1336.     'JPO  ', 'JL   ', 'JNGE ', 'JNL  ', 'JGE  ', 'JLE  ',
  1337.     'JNG  ', 'JNLE ', 'JG   ', 'JC   ', 'JNC  ');
  1338.  
  1339.   opcode : opfield = (
  1340.     $70, $71, $72, $72, $73, $73, $74, $74, $75, $75, $76, $76,
  1341.     $77, $77, $e0, $e1, $e1, $e2, $e3, $78, $79, $7a, $7a, $7b,
  1342.     $7b, $7c, $7c, $7d, $7d, $7e, $7e, $7f, $7f, $72, $73);
  1343.  
  1344. begin shortjmp := False;
  1345. for I := 0 to numjmp do
  1346.   if Str = jumps[I] then
  1347.     begin
  1348.     InsertByte(opcode[I]);
  1349.     shortjmp := True;
  1350.     NoAddrs := True;
  1351.     NextA;
  1352.     if sym = identifier then
  1353.       begin
  1354.       if FindLabel(B) then
  1355.         begin
  1356.         Addr := B-(ByteCount+1);
  1357.         if Addr+$80 <= $ff then InsertByte(Lo(Addr))
  1358.         else Error(Chi, 'Too Far');
  1359.         end
  1360.       else
  1361.         begin               {enter jump into fixups}
  1362.         New(pf);
  1363.         with pf^ do
  1364.           begin
  1365.           next := firstfix;
  1366.           if firstfix <> nil then
  1367.             firstfix^.prev := pf;
  1368.           firstfix := pf;
  1369.           prev := nil;
  1370.           jmptype := short;
  1371.           name := symname;
  1372.           fix_pt := ByteCount; indx := tindex;
  1373.           InsertByte(0);     {dummy insertion}
  1374.           end;
  1375.         end;
  1376.       NextA;
  1377.       end
  1378.     else Error(Chi, 'Label Exp');
  1379.     end;
  1380. end;
  1381.  
  1382. {-------------ShfRot}
  1383. FUNCTION ShfRot : Boolean;
  1384. type
  1385.   instype = (rclx, rcrx, rolx, rorx, salx, sarx, shlx, shrx);
  1386.   nametype = array[rclx..shrx] of array[1..3] of Char;
  1387.   codetype = array[rclx..shrx] of Byte;
  1388. var
  1389.   inst : instype;
  1390.   cl : Byte;
  1391.  
  1392. const
  1393.   instname : nametype = (
  1394.     'RCL', 'RCR', 'ROL', 'ROR', 'SAL', 'SAR',
  1395.     'SHL', 'SHR');
  1396.  
  1397.   regcode : codetype = ($10, $18, 0, 8, $20, $38, $20, $28);
  1398.  
  1399. begin ShfRot := False;
  1400. if Lsid[0] = Chr(3) then
  1401.   for inst := rclx to shrx do
  1402.     if id3 = instname[inst] then
  1403.       begin
  1404.       NoAddrs := True; ShfRot := True;
  1405.       NextA;
  1406.       InsertByte($d0);       {may get modified later}
  1407.       if register(reg1, w1) then
  1408.         InsertByte($c0+regcode[inst]+reg1)
  1409.       else if MemReg(w2) then
  1410.         begin
  1411.         chk_bwptr;
  1412.         w1 := Ord(ByWord);
  1413.         InsertByte(modebyt+regcode[inst]);
  1414.         displace_bytes(w2);
  1415.         end
  1416.       else Error(Chi, 'Reg or Mem Exp');
  1417.       if sym = comma then NextA;
  1418.       cl := 0;
  1419.       if (id3 = 'CL ') then cl := 2
  1420.       else if nvalue <> 1 then Error(Chi, 'CL or 1 Exp');
  1421.       NextA;
  1422.       modify_byte(tindex0, cl+w1); {modify the opcode}
  1423.       end;
  1424. end;
  1425.  
  1426. {-------------CallJmp}
  1427. FUNCTION calljmp : Boolean;
  1428. type instype = (call, jmp);
  1429.   codetype = array[call..jmp] of Byte;
  1430. var
  1431.   inst : instype;
  1432.   dist : (nodist, long, shrt, near);
  1433.   tmp : Byte;
  1434.   dwtmp : ptrtype;
  1435.   B : Integer;
  1436.  
  1437. const
  1438.   shortop : codetype = ($e8, $e9);
  1439.   longop : codetype = ($9a, $ea);
  1440.   longcode : codetype = ($18, $28);
  1441.   shortcode : codetype = ($10, $20);
  1442.  
  1443. begin calljmp := False;
  1444. if Str = 'CALL ' then inst := call
  1445. else if Str = 'JMP  ' then inst := jmp
  1446. else Exit;
  1447.  
  1448. calljmp := True;
  1449. NextA;
  1450. dist := nodist;
  1451. dwtmp := ByWord;            {could have passed a 'DWORD PTR' here}
  1452. if sym = jmpdist then
  1453.   begin
  1454.   if id2 = 'FA' then dist := long
  1455.   else if id2 = 'NE' then dist := near
  1456.   else if id2 = 'SH' then dist := shrt;
  1457.   NextA;
  1458.   end;
  1459. if (sym = address) then
  1460.   begin
  1461.   InsertByte(longop[inst]);
  1462.   InsertWord(nvalue);
  1463.   InsertWord(segm);
  1464.   end
  1465. else if sym = identifier then
  1466.   begin
  1467.   if dist = long then Error(Chi, 'Far not Permitted with Label');
  1468.   if FindLabel(B) then
  1469.     begin
  1470.     Addr := B-(ByteCount+2);
  1471.     if inst = call then
  1472.       begin
  1473.       InsertByte($e8);
  1474.       InsertWord(Addr-1);
  1475.       end
  1476.     else
  1477.       if (Addr+$80 <= $ff) and (dist <> near) then {jmp}
  1478.         begin               {short jump}
  1479.         InsertByte($eb); InsertByte(Lo(Addr));
  1480.         end
  1481.       else
  1482.         begin
  1483.         InsertByte($e9); InsertWord(Addr-1);
  1484.         end;
  1485.     end                     {findlabel}
  1486.   else
  1487.     begin                   {enter it into fixup chain}
  1488.     New(pf);
  1489.     with pf^ do
  1490.       begin
  1491.       next := firstfix;
  1492.       if firstfix <> nil then
  1493.         firstfix^.prev := pf;
  1494.       firstfix := pf;
  1495.       prev := nil;
  1496.       name := symname;
  1497.       if dist = shrt then
  1498.         begin
  1499.         jmptype := short;
  1500.         InsertByte($eb);
  1501.         fix_pt := ByteCount; indx := tindex;
  1502.         InsertByte(0);       {dummy insertion}
  1503.         end
  1504.       else
  1505.         begin
  1506.         jmptype := med;
  1507.         if inst = call then InsertByte($e8) else InsertByte($e9);
  1508.         fix_pt := ByteCount; indx := tindex;
  1509.         InsertByte(0);       {dummy insertion}
  1510.         indx2 := tindex;
  1511.         InsertByte(0);       {another dummy byte}
  1512.         end;
  1513.       end;
  1514.     end;
  1515.   end                       {identifier}
  1516. else if register(reg1, w1) then
  1517.   begin
  1518.   if w1 = 0 then wordreg;
  1519.   if dist = long then Error(Chi, 'FAR not Permitted');
  1520.   InsertByte($ff);
  1521.   InsertByte($c0+shortcode[inst]+reg1);
  1522.   end
  1523. else if MemReg(w1) then
  1524.   begin
  1525.   if (dist = long) or (dwtmp = dwptr) then tmp := longcode[inst]
  1526.   else tmp := shortcode[inst];
  1527.   InsertByte($ff);
  1528.   InsertByte(modebyt+tmp);
  1529.   displace_bytes(w1);
  1530.   end
  1531. else errnull;
  1532. NextA;
  1533. end;
  1534.  
  1535. {-------------retrn}
  1536. PROCEDURE retrn(far : Boolean);
  1537. begin
  1538. if (sym = disp16) or (sym = disp8) then
  1539.   begin
  1540.   if far then InsertByte($ca) else InsertByte($c2);
  1541.   InsertWord(nvalue);
  1542.   NextA;
  1543.   end
  1544. else begin
  1545. if far then InsertByte($cb) else InsertByte($c3);
  1546. end;
  1547. end;
  1548.  
  1549. {-------------otherinst}
  1550. FUNCTION otherinst : Boolean;
  1551. label 2, 10, 20, 30;
  1552. type
  1553.   instsym = (ret, retf, aam, aad, inn, out, mul, imul, divd, idiv, Int);
  1554.   nametype = array[ret..Int] of array[1..5] of Char;
  1555. var index : instsym;
  1556.   tmp : Byte;
  1557. const instname : nametype = (
  1558.   'RET  ', 'RETF ', 'AAM  ', 'AAD  ', 'IN   ', 'OUT  ', 'MUL  ',
  1559.   'IMUL ', 'DIV  ', 'IDIV ', 'INT  ');
  1560.  
  1561.   PROCEDURE MulDiv(B : Byte);
  1562.   var wordbit : Integer;
  1563.   begin
  1564.   InsertByte($f6);
  1565.   if register(reg2, w2) then
  1566.     begin
  1567.     InsertByte($c0+B+reg2);
  1568.     wordbit := w2;
  1569.     end
  1570.   else if MemReg(w2) then
  1571.     begin
  1572.     chk_bwptr;
  1573.     wordbit := Ord(ByWord);
  1574.     InsertByte(modebyt+B);
  1575.     displace_bytes(w2);
  1576.     end
  1577.   else Error(Chi, 'Reg or Mem Exp');
  1578.   modify_byte(tindex0, wordbit);
  1579.   end;
  1580.  
  1581.   FUNCTION dxreg : Boolean;
  1582.   begin
  1583.   dxreg := False;
  1584.   if sym = identifier then
  1585.     if id2 = 'DX' then
  1586.       begin dxreg := True; NextA; end;
  1587.   end;
  1588.  
  1589.   FUNCTION accum(var W : Integer) : Boolean;
  1590.   var result_acc : Boolean;
  1591.     {See if next is AL or AX}
  1592.   begin
  1593.   if (sym = identifier) then
  1594.     begin
  1595.     result_acc := (id3 = 'AX ') or (id3 = 'AL ');
  1596.     if result_acc then
  1597.       begin
  1598.       if Str[2] = 'X' then W := 1 else W := 0; {word vs byte register}
  1599.       NextA;
  1600.       end;
  1601.     end;
  1602.   accum := result_acc;
  1603.   end;
  1604.  
  1605. begin
  1606. otherinst := False;
  1607. for index := ret to Int do
  1608.   if Str = instname[index] then goto 2;
  1609. Exit;
  1610.  
  1611. 2: otherinst := True; NextA;
  1612. case index of
  1613.   ret : retrn(False);
  1614.   retf : retrn(True);
  1615.   out : begin
  1616.         if dxreg then InsertByte($ee) {out dx,ac}
  1617.         else if sym = disp8 then
  1618.           begin             {out port,ac}
  1619.           InsertByte($e6);
  1620.           InsertByte(Lo(nvalue));
  1621.           NextA;
  1622.           end
  1623.         else goto 10;
  1624.         if sym = comma then NextA;
  1625.         if accum(w1) then
  1626.           modify_byte(tindex0, w1) {al or ax}
  1627.         else goto 20;
  1628.         end;
  1629.   inn : begin
  1630.         if accum(w1) then
  1631.           begin
  1632.           if sym = comma then NextA;
  1633.           if dxreg then InsertByte($ec+w1) {in ac,dx}
  1634.           else
  1635.             begin
  1636.             if sym = disp8 then
  1637.               begin         {in ac,port}
  1638.               InsertByte($e4+w1);
  1639.               InsertByte(Lo(nvalue));
  1640.               NextA;
  1641.               end
  1642.             else
  1643.               10:Error(Chi, 'DX or Port Exp');
  1644.             end
  1645.           end
  1646.         else
  1647.           20:Error(Chi, 'AX or AL Exp');
  1648.         end;
  1649.   aam : begin
  1650.         tmp := $d4;
  1651.         goto 30;
  1652.         end;
  1653.   aad : begin
  1654.         tmp := $d5;
  1655.         30 : InsertByte(tmp);
  1656.         InsertByte($a);
  1657.         end;
  1658.   mul : MulDiv($20);
  1659.   imul : MulDiv($28);
  1660.   divd : MulDiv($30);
  1661.   idiv : MulDiv($38);
  1662.   int : begin
  1663.         if sym = disp8 then
  1664.           begin
  1665.           if nvalue = 3 then InsertByte($cc)
  1666.           else
  1667.             begin
  1668.             InsertByte($cd);
  1669.             InsertByte(Lo(nvalue));
  1670.             end;
  1671.           NextA;
  1672.           end
  1673.         else errnull;
  1674.         end;
  1675.  end;
  1676. end;
  1677.  
  1678. {-------------getquoted}
  1679. FUNCTION getquoted(var ls : bigstring) : Boolean;
  1680. var SaveChi, k : Integer;
  1681.   term : Char;
  1682.   gq : Boolean;
  1683. begin
  1684. skipspaces;
  1685. SaveChi := Chi; k := 1;
  1686. gq := False;
  1687. if (Uch = '''') or (Uch = '"') then
  1688.   begin
  1689.   term := Uch; GetCh;
  1690.   while (Uch <> term) and (Uch <> Chr(cr)) do
  1691.     if (Uch <> Chr(cr)) and (k <= bigstringsize) then
  1692.       begin
  1693.       ls[k] := Lch; k := k+1; GetCh;
  1694.       end;
  1695.   GetCh;                    {pass by term}
  1696.   gq := not(Uch in ['+', '-', '*', '/']); {else was meant to be expr}
  1697.   end;
  1698. ls[0] := Chr(k-1);
  1699. if not gq then
  1700.   begin Chi := SaveChi-1; GetCh; end;
  1701. getquoted := gq;
  1702. end;
  1703.  
  1704. {-------------databyte}
  1705. PROCEDURE databyte;
  1706. var I : Integer;
  1707.   Lst : bigstring;
  1708. begin
  1709. repeat
  1710.   if getquoted(Lst) then
  1711.     begin
  1712.     for I := 1 to Ord(Lst[0]) do
  1713.       InsertByte(Lo(Ord(Lst[I])));
  1714.     end
  1715.   else
  1716.     if readbyte then InsertByte(byt)
  1717.     else begin errnull; end;
  1718.   skipspaces;
  1719. until (Uch = Chr(cr)) or (Uch = ';') or aerr;
  1720. NextA;
  1721. end;
  1722.  
  1723. {-------------chk_for_label}
  1724. PROCEDURE chk_for_label;
  1725. begin
  1726. if not prefix then          {could be prefix here}
  1727.   begin
  1728.   skipspaces;
  1729.   if (Lsid[0] > Chr(0)) and (Uch = ':') then
  1730.     begin                   {label found}
  1731.     GetCh; symname := Lsid;
  1732.     pl := firstlabel;       {check for duplication of label}
  1733.     while pl <> nil do
  1734.       with pl^ do
  1735.         begin
  1736.         if symname = name then Error(Chi, 'Duplicate Label');
  1737.         pl := next;
  1738.         end;
  1739.     New(pl);                {add the label to the label chain}
  1740.     with pl^ do
  1741.       begin
  1742.       next := firstlabel;
  1743.       firstlabel := pl;
  1744.       bytecnt := ByteCount;
  1745.       name := symname;
  1746.       end;
  1747.     pf := firstfix;         {see if any fixups are required}
  1748.     while pf <> nil do
  1749.       with pf^ do
  1750.         begin
  1751.         if name = symname then
  1752.           begin             {remove this fixup from chain}
  1753.           if pf = firstfix then
  1754.             firstfix := next
  1755.           else prev^.next := next;
  1756.           if next <> nil then next^.prev := prev;
  1757.           Dispose(pf);
  1758.           Addr := ByteCount-(fix_pt+1);
  1759.           if jmptype = short then
  1760.             begin
  1761.             if Addr+$80 <= $ff then modify_byte(indx, Lo(Addr))
  1762.             else Error(Chi, 'Too Far');
  1763.             end
  1764.           else
  1765.             begin           {jmptype=med}
  1766.             Addr := Addr-1;
  1767.             modify_byte(indx, Lo(Addr));
  1768.             modify_byte(indx2, Hi(Addr));
  1769.             end;
  1770.           end;
  1771.         pf := next;
  1772.         end;
  1773.     getstring;              {for next item to use}
  1774.     end;                    {label found}
  1775.   end                       {neither a label or a prefix}
  1776. else getstring;             {it was a prefix}
  1777. end;
  1778.  
  1779. {-------------interpret}
  1780. PROCEDURE interpret;
  1781. begin
  1782. tindex0 := tindex;          {opcode position}
  1783. getstring;
  1784. chk_for_label;
  1785. while prefix do             {process any prefix instructions}
  1786.   getstring;
  1787. if Lsid[0] > Chr(0) then
  1788.   begin
  1789.   if not NoOperand then
  1790.     if not OneOperand then
  1791.       if not TwoOperands then
  1792.         if not shortjmp then
  1793.           if not calljmp then
  1794.             if not ShfRot then
  1795.               if not otherinst then
  1796.                 if not faddtype then
  1797.                   if not fnoperand then
  1798.                     if not fiaddtype then
  1799.                       if not fldtype then
  1800.                         if not fmemonly then
  1801.                           if not fildtype then
  1802.                             if not fstionly then
  1803.                               if id3 = 'DB ' then databyte else
  1804.                                 if Lsid = 'END' then
  1805.                                   begin
  1806.                                   TheEnd := True;
  1807.                                   NextA;
  1808.                                   end
  1809.                                 else Error(Chi, 'Unknown Instruction');
  1810.   end
  1811. else NextA;                 {if not a string find out what}
  1812. if sym <> EOLsym then Error(Chi, 'End of Line Exp');
  1813. end;
  1814.  
  1815. {-------------chk_ioerror}
  1816. FUNCTION chk_ioerror(S : filestring): Integer;
  1817. var ioerr : Integer;
  1818. begin
  1819. ioerr := IOResult;
  1820. if ioerr = 1 then WriteLn('Can''t find ', S)
  1821. else if ioerr <> 0 then WriteLn('I/O Error ', Hex4(ioerr));
  1822. chk_ioerror := ioerr;
  1823. end;
  1824.  
  1825. {-------------PromptForInput}
  1826. PROCEDURE PromptForInput;
  1827. var
  1828.   inname,name : filestring;
  1829.   err : Integer;
  1830. begin
  1831. {$I-}
  1832. Repeat
  1833.   Write('Source Filename [.ASM]: '); ReadLn(inname);
  1834.   if inname='' then Halt;
  1835.   DefaultExtension('ASM', inname, name);
  1836.   Assign(inn, inname); Reset(inn);
  1837.   err:=chk_ioerror(inname);
  1838.   if err>1 then Halt(1);
  1839. until err=0;
  1840. Write('Object Filename [', name, '.OBJ]: '); ReadLn(inname);
  1841. if inname='' then inname:=name;   {Use the same name}
  1842. DefaultExtension('OBJ',inname,name);
  1843. Assign(out, inname);
  1844. ReWrite(out);
  1845. if chk_ioerror(inname)<>0 then Halt(1);
  1846. {$I+}
  1847. end;
  1848.  
  1849. {-------------CommandInput}
  1850. PROCEDURE CommandInput;
  1851. var
  1852.   inname,name : filestring;
  1853.  
  1854.   PROCEDURE DoHelp;
  1855.   begin
  1856.   Halt;
  1857.   end;
  1858.  
  1859. begin
  1860. inname:=ParamStr(1);
  1861. if Pos('?', inname)<>0 then DoHelp;
  1862. DefaultExtension('ASM', inname, name);
  1863. {$I-}
  1864. Assign(inn, inname);
  1865. ReSet(inn);
  1866. if chk_ioerror(inname)<>0 then Halt(1);
  1867. if ParamCount>=2 then inname:=ParamStr(2)
  1868.   else inname:=name;             {Use the old name}
  1869. DefaultExtension('OBJ',inname,name);
  1870. Assign(out, inname);
  1871. ReWrite(out);
  1872. if chk_ioerror(inname)<>0 then Halt(1);
  1873. {$I+}
  1874. end;
  1875.  
  1876. {-------------main}
  1877. begin
  1878. Write(signon1); WriteLn(signon2);
  1879.  
  1880. start_col := 1; TheEnd := False;
  1881. tindex := 0;
  1882. ByteCount := 0;
  1883. firstlabel := nil; firstfix := nil;
  1884. InsertStr('Inline('+^m^j);
  1885. str_start := True;
  1886.  
  1887. if ParamCount >= 1 then CommandInput else PromptForInput;
  1888.  
  1889. while not EoF(inn) and not TheEnd do
  1890.   begin
  1891.   aerr := False; NoAddrs := False;
  1892.   ByWord := unkptr;
  1893.   column := 0;
  1894.   ReadLn(inn, st); Chi := 1; GetCh; sym := othersym;
  1895.   if st <> '' then
  1896.     begin
  1897.     InsertStr('  ');
  1898.     interpret;
  1899.     while column < CommentColumn do InsertChr(' ');
  1900.     InsertChr('{');
  1901.     I := 1;
  1902.     while (column < 124) and (I <= Length(st)) do
  1903.       begin
  1904.       InsertChr(st[I]);
  1905.       I := I+1;
  1906.       end;
  1907.     InsertStr('}'^m^j);
  1908.     end;
  1909.   end;
  1910. InsertStr(');'^m^j);
  1911. pf := firstfix;               {report any fixups not made}
  1912. while pf <> nil do
  1913.   with pf^ do
  1914.     begin
  1915.     WriteLn('Label not Found-- ', name);
  1916.     pf := next;
  1917.     end;
  1918. for I := 0 to tindex-1 do Write(out, TextArray[I]);
  1919. Close(out);
  1920. Close(inn);
  1921. end.
  1922.